home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Emulator / Tests / qsort.pl < prev    next >
Encoding:
Text File  |  1989-04-14  |  961 b   |  43 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. foreign_file('random.o',[get_random,set_random]).
  5. foreign(get_random, c, get_random([-integer])).
  6. foreign(set_random, c, set_random(+integer)).
  7.  
  8. init :- load_foreign_files(['random.o'], []),
  9.     abolish(foreign_file, 2),
  10.     abolish(foreign, 3).
  11.  
  12. main :-
  13.     set_random(23),
  14.     make_list(20000,L),
  15.     qsort(L,X,[]),
  16.     write_limited(20,X), nl.
  17.  
  18. qsort([X|L],R,R0) :-
  19.     partition(L,X,L1,L2),
  20.     qsort(L2,R1,R0),
  21.     qsort(L1,R,[X|R1]).
  22. qsort([],R,R).
  23.  
  24. partition([X|L],Y,[X|L1],L2) :-
  25.     X<Y, !,
  26.     partition(L,Y,L1,L2).
  27. partition([X|L],Y,L1,[X|L2]) :-
  28.     partition(L,Y,L1,L2).
  29. partition([],_,[],[]).
  30.  
  31. make_list(0,[]) :- !.
  32. make_list(N,[X|Xs]) :-
  33.     get_random(X),
  34.     N1 is N -1,
  35.     make_list(N1,Xs).
  36.  
  37. write_limited(N,X) :- write('['), write_limited2(N,X), write('...]'), nl.
  38. write_limited2(0,_) :- !.
  39. write_limited2(_,[]) :- !.
  40. write_limited2(N,[X|Xs]) :- N1 is N - 1, 
  41.     write(X), write(','), 
  42.     write_limited2(N1,Xs).
  43.